ComputeSpatialAverageSnow Subroutine

public subroutine ComputeSpatialAverageSnow(dt, rain, swe, meltCoeff, freeWater, snowMelt)

Compute spatial average of snow variables

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: dt

time step (s)

type(grid_real), intent(in) :: rain

liquid precipitation rate (m/s)

type(grid_real), intent(in) :: swe

snow water equivalent (m)

type(grid_real), intent(in) :: meltCoeff

melt coefficient (mm/day/°C)

type(grid_real), intent(in) :: freeWater

liquid water in snow (m)

type(grid_real), intent(in) :: snowMelt

snow melt (m)


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: c
integer(kind=short), public :: count
integer(kind=short), public :: i
integer(kind=short), public :: r
real(kind=float), public :: snowarea

Source Code

SUBROUTINE ComputeSpatialAverageSnow   & 
!
 (dt, rain, swe, meltCoeff, freeWater, snowMelt)  

IMPLICIT NONE

!arguments with intent in:
INTEGER (KIND = short), INTENT(IN) :: dt !!time step (s) 
TYPE (grid_real), INTENT(IN) :: rain !! liquid precipitation rate (m/s) 
TYPE (grid_real), INTENT(IN) :: swe !! snow water equivalent (m)
TYPE (grid_real), INTENT(IN) :: meltCoeff !! melt coefficient (mm/day/°C)
TYPE (grid_real), INTENT(IN) :: freeWater !! liquid water in snow (m)
TYPE (grid_real), INTENT(IN) :: snowMelt !!snow melt  (m)

!DEBUG intent(inout) to let modify grid_mapping



!local declarations
INTEGER (KIND = short) :: i, r, c
INTEGER (KIND = short) :: count
REAL (KIND = float)    :: snowarea ![m2]
!-------------------------------end of declaration-----------------------------

!DEBUG
!force gridmapping on snow maps
!remeber to remove it after new release of snow module will be 
!developed that sets CRS properly
!swe % grid_mapping = rain % grid_mapping
!water % grid_mapping = rain % grid_mapping

DO i = 1, nextents
    count = 0

    !rainfall (precipitation liquid fraction)
    IF ( snowout (1) ) THEN
      count = count + 1
      extents (i) % snow (count) = &
            GetMean (rain,  maskInteger = extents (i) % mask ) * &
            dt * 1000. !conversion to mm over dt
    END IF

    !snow water equivalent
    IF ( snowout (2) ) THEN
      count = count + 1
      extents (i) % snow (count) = &
            GetMean (swe,  maskInteger = extents (i) % mask ) * 1000.
    END IF

    !snow melt coefficient
    IF ( snowout (3) ) THEN
      count = count + 1
      extents (i) % snow (count) = &
            GetMean (meltCoeff,  maskInteger = extents (i) % mask )
    END IF

    !snow covered percentage
    IF ( snowout (4) ) THEN
      !compute snow covered area
      snowarea = 0.
      DO r = 1, extents (i) % mask % idim
         DO c = 1, extents (i) % mask % jdim
            IF (extents (i) % mask % mat (r,c) /= extents (i) % mask % nodata) THEN
               IF (swe % mat (r,c) > 0.) THEN
                   snowarea = snowarea +  CellArea (extents (i) % mask, r, c)
               END IF
            END IF
         END DO
      END DO
      !compute snow covered percentage
      count = count + 1
      extents (i) % snow (count) = snowarea / extents (i) % area
    END IF
    
    !water in snow
    IF ( snowout (5) ) THEN
      count = count + 1
      extents (i) % snow (count) = &
            GetMean (freeWater,  maskInteger = extents (i) % mask ) * 1000.
    END IF
    
    !snow melt
    IF ( snowout (6) ) THEN
      count = count + 1
      extents (i) % snow (count) = &
            GetMean (snowMelt,  maskInteger = extents (i) % mask ) * 1000.
    END IF
      
END DO

RETURN
END SUBROUTINE ComputeSpatialAverageSnow